home *** CD-ROM | disk | FTP | other *** search
/ Night Owl 9 / Night Owl CD-ROM (NOPV9) (Night Owl Publisher) (1993).ISO / 042a / swags_z.zip / SCREEN.SWG < prev    next >
Text File  |  1993-05-28  |  30KB  |  1 lines

  1. SWAGOLX.EXE (c) 1993 GDSOFT  ALL RIGHTS RESERVED 00017         SCREEN HANDLING ROUTINES                                          1      05-28-9313:56ALL                      SWAG SUPPORT TEAM        CLRSCR1.PAS              IMPORT              7           Procedure fillWord(Var dest; count, data: Word);πbeginπ  Inline(π    $C4/$BE/dest/          { les di, dest[bp] }π    $8B/$8E/count/         { mov cx, count[bp] }π    $8B/$86/data/          { mov ax,data[bp] }π    $FC/                   { cld }π    $F3/$AB                { rep stosw }π  )πend;ππProcedure ClrScr;πVarπ  screen: Array[1..25, 1..80, 1..2] of Char Absolute $b800:$0000;πbeginπ  fillWord(screen, sizeof(screen) div 2, $0720)πend;ππ{ or }ππProcedure ClrScr;πTypeπ  TScreen: Array[1..25, 1..80, 1..2] of Char;πVarπ  VideoSegment: Word;πbeginπ  if (MemW[$40:$10] and $30)=$30 thenπ    VideoSegment:=$B000π  elseπ    VideoSegment:=$B800;π  fillWord(ptr(VideoSegment, 0)^, sizeof(TScreen) div 2, $0720)πend;                                                      2      05-28-9313:56ALL                      SWAG SUPPORT TEAM        CLRSCR2.PAS              IMPORT              4           {π>How do you Write a clear screen Procedure in standard pascal forπ>the vax system?  I talking about a nice clear screen prgm that does'tπ>scroll everything off the screen.  Something that works in a flash..π}ππConstπ  clear_screen = CHR(27) + CHR(91) + CHR(50) +CHR(74);ππbeginπ  Write(clear_screen);π  readln;πend.                                                                   3      05-28-9313:56ALL                      SWAG SUPPORT TEAM        CLRSCR3.PAS              IMPORT              7           {πMICHAEL NICOLAIππYou want to clear the entire screen? Then just Write 00 in every Byte!πYou have to save the screen first, of course. :-)ππThis Procedure saves the screen, clears it, waits For a keystroke andπthen restores the screen:π}ππUsesπ  Crt;ππProcedure ClearScreen;πConstπ  lines = 50;   { number of lines }π  length = 160 * lines - 1;πVarπ  i      : Word;π  screen : Array [0..length] of Byte;πbeginπ { save the screen }π For i := 0 to length doπ  screen[i] := mem[$B800 : i];π { blank screen }π For i := 0 to length doπ  mem[$B800 : i] := 0;π { wait For keystroke }π While (NOT KeyPressed) do;π { restore screen }π For i := 0 to length doπ  mem[$B800 : i] := screen[i];πend;ππbeginπ  ClearScreen;πend.π                                                      4      05-28-9313:56ALL                      SWAG SUPPORT TEAM        DUALOUT1.PAS             IMPORT              21          {π> Who knows how to detect and access dual display's?ππAs this feature is only available if you're using VGA as the primary adapterπyou can get information about a second adapter by interrupt 10h.ππ        Get primary/secondary video adapter:π        interrupt:      10hπ        input:          AH = 1Ahπ                        AL = 00h                               (subFunction)π        output:         AL = 1Ah                (indicates Function support)π                        BL = code For active card              (primary one)π                        BH = code For inactive cardππ                        where following codes are valid:π                        00h     no cardπ                        01h     MDA With monochrome displayπ                        02h     CGA With CGA displayπ                        03h     reservedπ                        04h     EGA With EGA or multiscan displayπ                        05h     EGA With monochrome displayπ                        06h     reservedπ                        07h     VGA With monochrome displayπ                        08h     VGA With VGA or multiscan displayπ                        09h     reservedπ                        0Ah     MCGA With CGA display (PS/2)π                        0Bh     MCGA With monochrome display (PS/2)π                        0Ch     MCGA With color display (PS/2)π                        FFh     unknownππ        Set primary/secondary video adapter:π        interrupt:      10hπ        input:          AH = 1Ahπ                        AL = 01h                                (subFunction)π                        BL = code For active card        (here secondary one)π                        BH = code For inactive cardπ        output:         AH = 1Ah                 (indicates Function support)ππFirst you call subFunction 00h to get the code of your primary and secondaryπvideo adapter. Then you can toggle between them by using subFunction 01h.ππTo get back ontopic (Pascal code is needed ;-)) here's a simple example For aπtoggle Procedure:π}πUses Dos;ππProcedure ToggleAdapters;πVar Regs            : Registers;π    Active,Inactive : Byte;πbeginπ  Regs.AH := $1A;π  Regs.AL := $00;π  Intr($10,Regs);π  If Regs.AL=$1A Then           { is Function supported? (is VGA?) }π beginπ   Active   := Regs.BL;                      { exchange both codes }π   Inactive := Regs.BH;π   Regs.AH  := $1A;π   Regs.AL  := $01;π   Regs.BL  := Inactive;π   Regs.BH  := Active;π   Intr($10,Regs);                           { now you can't see me }π end;πend;π              5      05-28-9313:56ALL                      SWAG SUPPORT TEAM        GETCHAR1.PAS             IMPORT              12          {π│What would be the best way to find out what Character is at a certainπ│location on the screen.  For example, Lets say I went to locationπ│(10,2) and at that location is the letter 'S' now withoutπ│disturbing the letter S how can I determine if it is there or not?πππA 25-line by 80-column screen has 2,000 possible cursor positions. Theπ2,000 Words that begin at the memory location $B800:0000 (or $B000:0000 ifπyour machine is monochrome) define the current image. The first Byte ofπeach Word is the ASCII Character to be displayed, and the second Byte isπthe attribute of the display, which controls such Characteristics as colorπand whether it should blink....ππI you used the standard (X,Y) coordinate system to define a cursor positonπon the screen, With the upper left corner at (1,1) and lower right cornerπat (80,25), then With a lettle algebra you can see that the offset valueπFor a cursor position can be found at:ππ   Words:  80*(Y-1) + (X-1)πorπ   Bytes:  160*(Y-1) + 2*(X-1)πππHere's a Function that will return the Character at location (X,Y):ππ}πFunction GetChar(X,Y:Byte):Char;π  (* Returns the Character at location (X,Y) *)πConstπ  ColorSeg = $B800;     (* For color system *)π  MonoSeg  = $B000;     (* For mono system  *)πbeginπ  GetChar := Chr(Mem[ColorSeg:160*(Y-1) + 2*(X-1)])πend;π                                                                                                   6      05-28-9313:56ALL                      SWAG SUPPORT TEAM        GETCHAR2.PAS             IMPORT              9           {π>I need a routine that will go to a specific screen position and grab oneπ>or two Characters that are there (or next to it) - e.g It would go to rowπ>1 column 1 and return With the Character in that spot..ππTry this For TP 6.0π}ππUsesπ  Crt;ππFunction ScrnChar(x,y:Byte):Char;πVarπ  xkeep, ykeep : Byte;πbeginπ  xkeep := whereX;π  ykeep := whereY;π  GotoXY(x, y);π  Asmπ    push  bxπ    mov   ah,8π    xor   bx,bxπ    int   16π    mov   @Result,alπ    pop   bxπ  end;π  GotoXY(xkeep,ykeep)πend;π{πI am not sure about the "@Result" as being the correct name, but TP 6.0 has aπname that is used For the result of a Function. This should be Compatible withπthe Windows etc. of TP 6.0π}ππVarπ  ch : Char;π  Count : Integer;ππbeginπ  ClrScr;π  For Count := 1 to 500 doπ  beginπ    Write(chr(Count));π    if count mod 80 = 0 thenπ      Write(#13#10);π  end;π  ch := scrnChar(5,5);π  Write(#13#10#10#10#10#10,'The Character at position (5,5) is: ',ch);π  readln;πend.                                                              7      05-28-9313:56ALL                      SWAG SUPPORT TEAM        GETSTRNG.PAS             IMPORT              10          Unit scn_io;ππInterfaceππProcedure GetScreenStr(x, y, l: Integer; Var s: String);ππImplementationππProcedure GetChar(x, y: Integer; Var ch: Char);π(*** gets the Character from screen position x, y;π     x is horizontal co-ord, y is vertical;π     top left corner is 0,0 ***)πConstπ  base = $b800;            (* $b000 For mono *)πVarπ  screen_Byte: Byte;π  offs: Integer;πbeginπ  offs := ( (y*80) + x ) * 2;π  screen_Byte := mem[base: offs];π  ch := chr(screen_Byte);πend{proc..};ππProcedure PutChar(x, y: Integer; ch: Char);π(*** pits the Character ch to screen position x, y; ***)πConstπ  base = $b800;            (* $b000 For mono *)πVarπ  screen_Byte: Byte;π  offs: Integer;πbeginπ  offs := ( (y*80) + x ) * 2;π  screen_Byte := ord(ch);π  mem[base: offs] := screen_Byte;πend{proc..};ππProcedure GetScreenStr(x, y, l: Integer; Var s: String);π(*** gets the String from screen position x,y of length l ***)πVarπ  i: Integer;π  ch: Char;πbeginπ  s := '';π  For i := 1 to l doπ  beginπ    GetChar(x, y, ch);π    s := s + ch;π    inc(x);π    if x > 79 thenπ    beginπ      inc(y); x:= 0;π    end{if x >..};π  end{For i..}πend{proc..};ππend{Unit..}.π     8      05-28-9313:56ALL                      SWAG SUPPORT TEAM        SAVERES.PAS              IMPORT              10          Uses Dos,Crt;π{ saves and restores and area of screen }πConstπ   Max = 3;ππTypeπ   ScreenImage = Array[0..1999] of word;π   FrameRec    = Recordπ                    Upperleft    : Word;π                    LowerRight   : Word;π                    ScreenMemory : ScreenImage;π                 End;ππVARπ   SnapShot     : ^ScreenImage;π   FrameStore   : Array [1..10] of ^FrameRec;π   WindowNum    : Byte;ππProcedure OpenWindow(UpLeftX,UpLeftY,LoRightX,LoRightY : Byte);πBeginπ   SnapShot := Ptr( $B800, $0000);π   Inc(WindowNum);π   New(FrameStore[WindowNum]);π   WITH Framestore[WindowNum]^ doπ   Beginπ      ScreenMemory := SnapShot^;π      UpperLeft    := WindMin;π      LowerRight   := WindMax;π   end;π   Window(UpLeftX,UpLeftY,LoRightX,LoRightY);πend;ππProcedure CloseWindow;πBeginπ   With Framestore[WindowNum]^ doπ   Beginπ      Snapshot^ := ScreenMemory;π      Window ( (Lo(UpperLeft)+1), (Hi(UpperLeft)+1),π             (Lo(LowerRight)+1), (Hi(LowerRight)+1) );π   end;π   Dispose( Framestore[WindowNum]);π   Dec(WindowNum);πEnd;ππBeginπOpenWIndow(3,3,45,15);πClrScr;πReadkey;πCloseWindow;πEnd.π                                                9      05-28-9313:56ALL                      SWAG SUPPORT TEAM        SCRLTEXT.PAS             IMPORT              5           Usesπ  Crt;ππProcedure ScrollTextLine (x1, x2 : Integer ; y : Integer ; St : String) ;πbeginπ  While Length(St)<(x2-x1+1) Doπ    St:=St+' ' ;π  While not KeyPressed Doπ    beginπ      GotoXY(x1, y) ;π      Write(Copy(St, 1, x2-x1+1)) ;π      Delay(100) ;π      St:=Copy(St, 2, Length(St)-1)+St[1] ;π    end ;πend ;ππbeginπ  ClrScr;π  TextColor(lightgreen);π  scrollTextline(10,60,12,'Hello There!');πend.                                                                                                            10     05-28-9313:56ALL                      SWAG SUPPORT TEAM        SCRNSAVE.PAS             IMPORT              18          { GLEN WILSON }ππ{$m 2000,0,0}  (* Stops Pascal using all of memory *)π{$R-,s-,v-,b-,n-,l+}  (* Nothing important, helps keep the size down*)πProgram screensaver;  (* Only blanks screen on CGA/Mono not VGA/etc*)ππUsesπ  Dos, Crt;ππConstπ  TimerInt = $08;              {Timer Interrupt}π  KbdInt   = $09;              {Keyboard Interrupt}π  Timerlimit : Word = 5460;   {5 minute Delay}ππVarπ  Regs    : Registers;π  Cnt     : Word;π  PortNum : Word;π  PortOff : Word;π  Porton  : Word;π  OldKBDVEC   : Pointer;π  OldTimerVec : Pointer;π  i    : Real;π  code : Real;πππProcedure STI;πInline($FB);ππProcedure CLI;πInline($FA);ππProcedure CallOldInt(Sub : Pointer);π(* Primitive way of calling Old Interrupt, never the less, you can see what isπ   happening! *)πbeginπInline($9c/           { PushF }π       $FF/$5e/$06);  { Call DWord PTR [BP+6] }πend;ππProcedure Keyboard(flags,CS,IP,AX,BX,CX,DX,SI,DI,DS,ES,BP : Word); Interrupt;ππbeginπ  CallOldInt(OldKbdVec);π  if (CNT >= Timerlimit) thenπ    port[portnum] := porton;π  Cnt := 0;π  STI;πend;ππProcedure Clock(flags,CS,IP,AX,BX,CX,DX,SI,DI,DS,ES,BP : Word); Interrupt;πbeginπ  CallOldInt(OldTimerVec);π  if (CNT > Timerlimit) thenπ    Port[portnum] := portoffπ  elseπ    Inc(Cnt);π  STI;πend;πππbeginπ Regs.AH := $0F;π INTR($10, regs); (* determine Type of video adapter (Mono or Cga) *)ππ  if Regs.AL= 7 thenπ  beginπ    Portnum := $3b8;π    Portoff := $21;π    PortOn  := $2d;π  endπ  elseπ  beginπ    Portnum:=$3d8;π    Portoff:=$25;π    porton :=$2d;π  end;ππ  (* Save original Procedures *)π  GetIntVec(KbdInt, OldKbdVEc);π  GetIntVec(TimerInt, OldTimerVec);ππ  (* Install new Interrupts *)π  SetIntVec(timerint, @clock);π  SetIntVec(KbdInt, @Keyboard);ππ  Cnt := 0; (* Initialize counter *)π  Keep(0); (* Tell Pascal to keep us in memory *)πend.ππ{πit seems rather complex but most of that crap is For turningπon and off the screen.  if you don't have a CGA or MONO you can replace theπPort crap With Writeln statements so you can see whats hapening.ππBTW This is an example from a Programming book ( can't remember what it isπcalled ) becareful, It might be covered by Copy right laws.π}π                               11     05-28-9313:56ALL                      SWAG SUPPORT TEAM        SCRWRIT1.PAS             IMPORT              19          {πDoes any one know of a way to Write 80 chrs to the bottom line of theπscreen without the screen advancing?ππYou're gonna have to Write directly to the screen : the problem is that,πwhen you use std ways to Write to the screen, the cursor is always oneπCharacter ahead of the Text you displayed... so standard display procsπcan not be used to Write to the 80th Character of the 25th line.ππHere is a simple proc to Write Text directly to the screen :π}ππConstπ     VideoSeg  : Word = $b800 ;    { Replace With $b000 if no color card }ππProcedure DisplayString(x, y : Byte; Zlika : String; Attr : Byte); Assembler ;ππ{ x and y are 0-based }πAsmπ  Mov  ES, VideoSeg        { Initialize screen segment adr }ππ  { Let's Compute the screen address of coordinates (x, y) }π  { Address:=(160*y)+(x ShL 2) ; }π  Mov  AL, 160             { 160 Bytes per screen line }π  Mul  Byte Ptr yπ  Mov  BL, xπ  Xor  BH, BHπ  ShL  BX, 1               { 2 Bytes per on-screen Character }π  Add  BX, AX              { BX contains offset where to display }ππ  { Initialize stuff... }π  Push DS                  { Save DS }π  ClD                      { String ops increment DI, SI }π  LDS  SI, Zlika           { DS:DI points to String }π  LodSB                    { Load String length in AL }π  Mov  CL, AL              { Copy it to CL }π  Xor  CH, CH              { CX contains String length }π  Mov  DI, BX              { DI contains address where to display }π  Mov  AH, Attr            { Attribute Byte in AH }π@Boucle:π  LodSB                    { Load next Char to display in AL }π  StoSW                    { Store Word (attr & Char) to the screen }π  Loop @Boucle             { Loop For all Chars }ππ  Pop  DS                  { Restore DS }πend ;ππ{πFurthermore, this is definitely faster than using Crt.Write...πI will ask those ones owning a CGA card to Forgive me, I ommited toπinclude the usual snow-checking... but this intends to be a shortπexample :-))πAlso note that there is no kind of checking, so you can Write out ofπthe screen if you want... but that's no good idea.πBTW, the attribute Byte value is Computed With the "magic Formula"πAttr:=Foreground_Color + (16 * Background_color) [ + 128 For blinking ]π}π                                                                                                 12     05-28-9313:56ALL                      SWAG SUPPORT TEAM        SCRWRIT2.PAS             IMPORT              21          {π SO> Got a question For you all out there..... How the heck can I Write aπ SO> Character  into the bottom right corner of a Window without the Windowπ SO> scrolling?π SO>π SO> if anyone knows some way to keep the Write command from Forwarding theπ SO> cursor  position Pointer, that would be fine enough For me.....ππSean, here is a way to do it without resorting to poking the screen.π}ππ{$A+,B+,D+,E-,F+,G-,I+,L+,N-,O+,P+,Q+,R+,S+,T-,V-,X+,Y+}π{$M 8192,0,0}ππUsesπ  Crt;πVarπ  index1, Index2: Byte;ππbeginπ  ClrScr;ππ{******************************************π First Write top line of bordered displayπ******************************************}ππ  Write ('╔');                     {Write top Left Corner}π  For Index1 := 1 to 78 do         {Write top Horizontal line }π    Write ('═');π  Write ('╗');                     {Write top Right Corner}ππ{*******************************************π Now Write Bottom line of bordered displayπ*******************************************}ππ  Write ('╚');                     {Write Bottom Left Corner}π  For Index1 := 1 to 78 do         {Write Bottom horizontal line}π    Write ('═');π  Write ('╝');                     {Write Bottom Right Corner}ππ{********************************************************************π Now inSERT 23 lines of Left&Right bordered display, pushing bottomπ line down as we doπ********************************************************************}ππ  For Index1 := 1 to 23 do begin   { Repeat 23 times }π    GotoXY (1, 2);                 {Move cursor back to Col 1, Line 2}π    InsLine;                       {Insert blank line (Scroll Text down)}π    Write ('║');                   {Write Left border vertical caracter}π    For Index2 := 1 to 78 do       {Write 78 spaces}π      Write (' ');π    Write ('║');                   {Write Right border vertical caracter}π  end;ππ{***********************************************************π I added this so the Program would pause For a key. This wayπ it will allow you to see that it does not scroll up sinceπ the cursor never Writes to position 25,80π***********************************************************}ππ  Asm                              {Assembler code to flush keyboard}π    mov Ax, 0C00h;π    Int 21h;π  end;π  ReadKey ;                        {Wait For a keypress}ππend.ππ{πBTW, this was written, Compiled and Tested in BP 7.0 but should work inπTP 4.0 and up if you remove the Assembler stuff.π}                                                                                                                             13     05-28-9313:56ALL                      SWAG SUPPORT TEAM        SPEEDVID.PAS             IMPORT              35          Unit SpeedVid;ππ{ High speed Text-video routines For working With binary Files, direct  }π{ screen access etc.  (c)1993 Chris Lautenbach                          }π{                                                                       }π{ You are hereby permitted to use this routines, so long as you give me }π{ credit.  If you modify them, do not distribute the modified version.  }π{                                                                       }π{ Notes:   This Unit will work fine in 50 line mode, or on monochrome   }π{          monitors.  Remember; when working in 50 line mode, always    }π{          make sure you call Window(1,1,80,50) so that WindMax is      }π{          updated With the correct screen co-ordinates.  In addition,  }π{          the ScrollScreen() routine is much faster than it's standard }π{          BIOS Int 10h counterpart.                                    }π{                                                                       }π{          Turbo Professional users have no need For FastWrite(),       }π{          VideoMode, or ScreenHeight - since these are approximations  }π{          are provided For use by people who do not have the TpCrt     }π{          Unit.                                                        }π{                                                                       }π{ If you need to contact me, I can be found in the NANet, City2City,    }π{ and Intelec Pascal echoes - or at my support BBS, Toronto Twilight    }π{ Communications (416) 733-9012. Internet: cs911212@iris.ariel.yorku.ca }ππInterfaceππUsesπ  Dos, Crt;ππConstπ  MonoMode : Boolean = False;ππTypeπ  ScreenLine = Array[1..160] of Char;π  ScreenBuffer = Array[1..50] of ScreenLine;π  DirectionType = (Up, Down);ππVarπ  VideoScreen : ScreenBuffer Absolute $B800:$0000;π  MonoScreen  : ScreenBuffer Absolute $B000:$0000;ππFunction  VideoMode : Byte;                               { Get video mode }πFunction  ScreenHeight : Byte;          { Return height of screen in lines }πProcedure ScrollScreen(Direction : DirectionType); { Scroll screen up/down }πProcedure FastWrite(st:String; x,y,color:Byte);    { Write Text to vid mem }πProcedure RestoreScreen(Var p:Pointer);             { Restore saved screen }πProcedure SaveScreen(Var p:Pointer);            { Save screen to a Pointer }ππImplementationππFunction VideoMode : Byte;πVarπ  Mode : Byte;πbeginπ  Asmπ    MOV AH, 0Fh              { Set Function to 0Fh - Get current video mode }π    INT 10h                  { Call interrupt 10h - Video Services }π    MOV Mode, AL             { Move INT 10h result to Mode Variable }π  end;π  VideoMode := Mode;πend;ππFunction ScreenHeight:Byte;πbeginπ  ScreenHeight := (Hi(WindMax) + 1);πend;ππProcedure ScrollScreen(Direction : DirectionType);πbeginπ  Case Direction ofπ    Up   :π      If MonoMode thenπ        Move(MonoScreen[2],MonoScreen[1],Sizeof(ScreenLine)*(ScreenHeight-1))π      ELSEπ        Move(VideoScreen[2],VideoScreen[1],Sizeof(ScreenLine)*(ScreenHeight-1));π    Down :π      If MonoMode thenπ        Move(VideoScreen[1],VideoScreen[2],Sizeof(ScreenLine)*(ScreenHeight-1))π      ELSEπ        Move(VideoScreen[1],VideoScreen[2],Sizeof(ScreenLine)*(ScreenHeight-1));π  end; { Case }πend;ππProcedure FastWrite(st:String; x,y,color:Byte);π{ Write a String directly to the screen, x=column, y=row }πVarπ  idx, cdx : Byte;πbeginπ  idx := x * 2;π  cdx := 1;π  Repeatπ    {$R-}π    If MonoMode thenπ    beginπ      MonoScreen[y][idx+2] := Chr(Color);π      MonoScreen[y][idx+1] := St[cdx];π    endπ    ELSEπ    beginπ      VideoScreen[y][idx+2] := Chr(Color);π      VideoScreen[y][idx+1] := St[cdx];π    end;π    {$R+}π    Inc(idx,2);π    Inc(cdx,1);π  Until cdx>=length(st);πend;ππProcedure RestoreScreen(Var p:Pointer);πbeginπ If Assigned(P) then  { make sure this Pointer IS allocated }π beginπ   If MonoMode thenπ     Move(P^, MonoScreen, 4000)π   ELSEπ     Move(P^, VideoScreen, ScreenHeight*SizeOf(ScreenLine));π   FreeMem(P,ScreenHeight*Sizeof(ScreenLine));π end;πend;ππProcedure SaveScreen(Var p:Pointer);πbeginπ  If not Assigned(P) then   { make sure Pointer isn't already allocated }π  beginπ    GetMem(P,ScreenHeight*Sizeof(ScreenLine));π    If MonoMode thenπ      Move(MonoScreen, P^, 4000)π    ELSEπ      Move(VideoScreen, P^, ScreenHeight*Sizeof(ScreenLine));π  end;πend;πππbeginπend.            14     05-28-9313:56ALL                      SWAG SUPPORT TEAM        TESTVID.PAS              IMPORT              29          Program TestVid;ππ{ High speed Text-video routines For working With binary Files, direct   }π{ screen access etc.  (c)1993 Chris Lautenbach                           }π{                                                                        }π{ You are hereby permitted to use this routines, so long as you give me  }π{ credit.  If you modify them, do not distribute the modified version.   }π{                                                                        }π{ This is the example Program, see SPEEDVID.PAS For the actual Unit      }π{ code, and usage information.                                           }π{                                                                        }π{ "ScreenFile" is a File containing sequential binary screen images. The }π{ easiest way to make these, is to draw several screens in a Program     }π{ like TheDraw, then save them as Binary.  After you are done, copy them }π{ all to one File, like so:                                              }π{                                                                        }π{ COPY /B SCREEN1.BIN+SCREEN2.BIN+SCREEN3.BIN SCREEN.BIN                 }π{                                                                        }π{ Note: the /B option is NECESSARY.  Without specifying binary mode,     }π{       COPY will insert ^Z's and other wierd stuff that will screw up   }π{       the resulting File.                                              }ππUses  Dos, Crt, SpeedVid;ππVar   ScreenFile : File of ScreenLine;π      StartLine, TempLine, idx : Integer;π      Cmd : Char;π      p : Pointer;ππProcedure ShowScreenLine(Index:Word);πbeginπ  If StartLine+Index<Filesize(ScreenFile) thenπ  beginπ    Seek(ScreenFile, StartLine+Index-1);π    Read(ScreenFile, VideoScreen[Index]);π  end;πend;ππbeginπ  MonoMode := (VideoMode = 7);π  SaveScreen(P);π  Assign(ScreenFile,'testvid.exe');π  {$I-} Reset(ScreenFile); {$I+}π  If IOResult<>0 thenπ  beginπ    Writeln('Error: Cannot open SCREEN.BIN.');π    Halt;π  end;π  StartLine:=0;π  For TempLine:=1 to ScreenHeight do ShowScreenLine(TempLine);π  Repeatπ    Repeat Until KeyPressed;π    Cmd:=ReadKey;π    If Cmd=#0 thenπ    beginπ      Cmd:=ReadKey;π      Case Cmd ofπ{Down}  #80 : If StartLine+1<Filesize(ScreenFile) thenπ              beginπ                Inc(StartLine);π                ScrollScreen(Up);π                ShowScreenLine(ScreenHeight);π              end;π{Up}    #72 : If StartLine-1>=0 thenπ              beginπ                Dec(StartLine);π                ScrollScreen(Down);π                ShowScreenLine(1);π              end;π{PgDn}  #81 : beginπ                If StartLine+ScreenHeight<Filesize(ScreenFile) thenπ                  TempLine:=ScreenHeightπ                    ELSEπ                  TempLine:=ScreenHeight-(Filesize(ScreenFile)-ScreenHeight);π                For idx:=1 to TempLine doπ                beginπ                  Inc(StartLine);π                  ScrollScreen(Up);π                  ShowScreenLine(ScreenHeight);π                end;π              end;π{PgUp}  #73 : beginπ                If StartLine-ScreenHeight>=0 thenπ                  TempLine:=ScreenHeightπ                    ELSEπ                  TempLine:=StartLine;π                For idx:=1 to TempLine doπ                beginπ                  Dec(StartLine);π                  ScrollScreen(Down);π                  ShowScreenLine(1);π                end;π              end;π      end; {case}π    end;π  Until Cmd=#27; {ESC}π  Close(ScreenFile);π  RestoreScreen(P);πend.π                                                         15     05-28-9313:56ALL                      SWAG SUPPORT TEAM        TEXTMODE.PAS             IMPORT              7           {π A small follow-up to the VGA tricks:π how about a 40x12 Textmode (posted earlier in the Assembler conference):π}ππProcedure Set12x40; Assembler;πAsmπ  MOV     AX, 1π  inT     $10            { activate 40x25 Text With BIOS }π  MOV     DX, $03D4      { CrtC }π  MOV     AL, 9          { maximum scan line register }π  OUT     DX, ALπ  inC     DXπ  in      AL, DXπ  or      AL, $80        { Double each scan-line   bit7 = 1 }π  OUT     DX, ALπ  MOV     AX, $0040      { set up BIOS data area access }π  MOV     ES, AXπ  MOV     AL, $0B        { BIOS txtlines on 12 = $B +1 }π  MOV     ES:[$0084], AL { so Programs like QEDIT will work With this }πend;ππ                                                                                                                   16     05-28-9313:56ALL                      SWAG SUPPORT TEAM        TEXTWDTH.PAS             IMPORT              13          { Keld Hansen }πProcedure SetCrtC; NEAR; Assembler;πConstπ  HorizParms : Array[1..2,1..7] of Word =π               (($6A00,$5901,$5A02,$8D03,$6004,$8505,$2D13),π                ($5F00,$4F01,$5002,$8203,$5504,$8105,$2813));πAsmπ  PUSH    DXπ  MOV     DX,ES:[0063h]π  PUSH    BXπ  MOV     AX,1110hπ  xor     CX,CXπ  INT     10hπ  POP     BXπ  MOV     AL,11hπ  OUT     DX,ALπ  INC     DXπ  in      AL,DXπ  DEC     DXπ  MOV     AH,ALπ  MOV     AL,11hπ  PUSH    AXπ  and     AH,7Fhπ  OUT     DX,AXπ  xor     BH,BHπ  SUB     BL,8π  NEG     BXπ  and     BX,14π  LEA     SI,[BX+OFFSET HorizParms]π  MOV     CX,7π@LOOP:  LODSWπ  OUT     DX,AXπ  LOOP    @LOOPπ  POP     AXπ  OUT     DX,AXπ  POP     DXπend;ππProcedure SetCharWidth(W : Word); Assembler;πAsmπ  MOV     ES,Seg0040π  MOV     BL,Byte PTR Wπ  MOV     BH,ES:[0085h]π  CALL    SetCrtCπ  MOV     DX,03C4hπ  MOV     AX,0100hπ  CLIπ  OUT     DX,AXπ  MOV     BX,0001hπ  CMP     W,8π  JE      @L01π  MOV     BX,0800hπ@L01:       MOV     AH,BLπ  MOV     AL,1π  OUT     DX,AXπ  MOV     AX,0300hπ  OUT     DX,AXπ  STIπ  MOV     BL,13hπ  MOV     AX,1000hπ  INT     10hπ  MOV     AX,1000hπ  MOV     BX,0F12hπ  INT     10hπ  xor     DX,DXπ  MOV     AX,720π  div     Wπ  MOV     ES:[004Ah],AXπend;ππ{πSetCharWidth can then be called With 8 (giving 90 Characters per line) or 9π(giving 80 Characters per line) after having switched into f.ex. 80x28 (byπselecting the appropriate number of scan lines and font size).π}π                                                                                  17     05-28-9313:56ALL                      SWAG SUPPORT TEAM        VIDEORAM.PAS             IMPORT              9           {πAuthor : BERNIE PALLEKππ> Thanks to those of you who have been answering my question aboutπ> writing to the last position on the far right bottom of the screen.π> As you will recall, the trouble I had was that when you Write to thatπ> position (position 80, line 25) using a Write (not a Writeln) statementππAnother solution would be to create a Procedure that directly Writes to theπvideo ram, like this:π}ππConstπ  vidSeg = $B800;  { $B000 For monochrome monitors }ππProcedure WriteAt(x1, y1 : Byte; msg : String);πVarπ  i : Integer;πbeginπ  For i := 1 to Length(msg) doπ    Mem[vidSeg : (x1 + i - 1) * 2 + (y1 - 1) * 160] := msg[i];πend;ππ{πThis will change the Text on any place on the screen, disregarding the cursorπposition.  Be careful, though!  if you Write a message With, say, 20πCharacters, and start it at 80, 25, only the first letter will be visible, andπthe rest of the String will over-Write other areas of ram, which could causeπmayhem!  Use With caution!π}